home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / ai.prl / dprolog.lha / dprolog.ari (.txt) < prev    next >
Microsoft Windows Help File Content  |  1991-03-05  |  30KB  |  630 lines

  1. :- write($
  2. d-Prolog - Arity Version 1.2
  3. Copyright (C) 1988 Donald Nute
  4. Advanced Computational Methods Center
  5. University of Georgia, Athens, GA  30602
  6.     reset_op,
  7.     op(1100,fx,@),
  8.     op(1100,fx,@@),
  9.     op(900,fx,neg ),
  10.     op(1100,xfy,:=),
  11.     op(1100,xfy,:^),
  12.     op(200,fx,list).
  13. /***********************************************************************
  14.  *                                                                     *
  15.  *  The clause 'true' is defeasibly derivable.  This is the termin-    *
  16.  *  ating condition for defeasible derivability.                       *
  17.  *                                                                     *
  18.  ***********************************************************************/
  19. defeasibly_derivable(true,_):- !.
  20. /***********************************************************************
  21.  *                                                                     *
  22.  *  A conjunction is defeasibly derivable if both conjuncts are.       *
  23.  *                                                                     *
  24.  ***********************************************************************/
  25. defeasibly_derivable((First,Rest),Clause):-
  26.     !,
  27.     defeasibly_derivable(First,Clause),
  28.     defeasibly_derivable(Rest,Clause).
  29. /***********************************************************************
  30.  *                                                                     *
  31.  *  Indefeasibly derivable goals are also defeasibly derivable.        *
  32.  *                                                                     *
  33.  ***********************************************************************/
  34. defeasibly_derivable(Goal,_):-
  35.     Goal.
  36. /***********************************************************************
  37.  *                                                                     *
  38.  *  A goal is defeasibly derivable if it is the consequent of a de-    *
  39.  *  feasible rule whose antecedent is defeasibly derivable and which   *
  40.  *  is not defeated by any competing rule or defeater.                 *
  41.  *                                                                     *
  42.  ***********************************************************************/
  43. defeasibly_derivable(Goal,_):-
  44.     (Goal := Condition),
  45.     defeasibly_derivable(Condition,Goal),
  46.     not defeat(Goal,Condition).
  47. /***********************************************************************
  48.  *                                                                     *
  49.  *  A goal is defeasibly derivable if a contrary is not indefeasibly   *
  50.  *  derivable and it is the consequent of an indefeasibly rule whose   *
  51.  *  consequent is defeasibly derivable.                                *
  52.  *                                                                     *
  53.  ***********************************************************************/
  54. defeasibly_derivable(Goal,_):-
  55.     clause(Goal,Condition),
  56.     Condition\=true,
  57.     defeasibly_derivable(Condition,Goal),
  58.     not Condition,
  59.     contrary(Goal,Contrary),
  60.     not Contrary.
  61. /***********************************************************************
  62.  *                                                                     *
  63.  *  We defeat a rule with consequent Head and condition Body if there  *
  64.  *  is a contrary of Head that defeats the rule.                       *
  65.  *                                                                     *
  66.  ***********************************************************************/
  67. defeat(Head,Body):-
  68.     contrary(Head,Contrary),
  69.     defeat(Head,Body,Contrary),
  70.     !.
  71. /***********************************************************************
  72.  *                                                                     *
  73.  *  A defeasible rule is always defeated by any indefeasibly deriv-    *
  74.  *  able contrary of its consequent.                                   *
  75.  *                                                                     *
  76.  ***********************************************************************/
  77. defeat(Head,Body,ContraryOfHead):-
  78.     ContraryOfHead,
  79.     !.
  80. /***********************************************************************
  81.  *                                                                     *
  82.  *  Next we look for a defeasible rule with a consequent that is a     *
  83.  *  contrary of the consequent of the defeasible rule we are trying    *
  84.  *  to defeat.  We compare the condition of this competing rule with   *
  85.  *  the body of the rule we are trying to defeat.  For the competing   *
  86.  *  rule to defeat the original rule, the antecedent of the competing  *
  87.  *  rule must be defeasibly derivable and must not be less informa-    *
  88.  *  tive than the antecedent of the original rule.                     *
  89.  *                                                                     *
  90.  ***********************************************************************/
  91. defeat(Head,Body,ContraryOfHead):-
  92.     (ContraryOfHead:=Condition),
  93.     not_more_informative(Body,Condition,Head,ContraryOfHead),
  94.     defeasibly_derivable(Condition,ContraryOfHead),
  95.     !.
  96. /***********************************************************************
  97.  *                                                                     *
  98.  *  This is exactly like the last procedure except that we try to use  *
  99.  *  a defeater to defeat the rule.                                     *
  100.  *                                                                     *
  101.  ***********************************************************************/
  102. defeat(Head,Body,ContraryOfHead):-
  103.     (ContraryOfHead:^Condition),
  104.     not_more_informative(Body,Condition,Head,ContraryOfHead),
  105.     defeasibly_derivable(Condition,ContraryOfHead),
  106.     !.
  107. /***********************************************************************
  108.  *                                                                     *
  109.  *  One last way a rule may be defeated by a contrary of itss conse-   *
  110.  *  quent is if the contrary is the consequent of some indefeasible    *
  111.  *  rule whose antecedent is defeasibly derivable.                     *
  112.  *                                                                     *
  113.  ***********************************************************************/
  114. defeat(Head,Body,ContraryOfHead):-
  115.     functor(ContraryOfHead,Predicate,_),
  116.     not system(Predicate),
  117.     clause(ContraryOfHead,Condition),
  118.     defeasibly_derivable(Condition,ContraryOfHead).
  119. /***********************************************************************
  120.  *                                                                     *
  121.  *  We want to know if one set of clauses is more informative than     *
  122.  *  another set of clauses.  We need this to decide which of two com-  *
  123.  *  peting rules to use.  We also keep track of the consequents of     *
  124.  *  the competing rules so we know what to tell the user if we find    *
  125.  *  a d-Prolog syntax error.                                           *
  126.  *                                                                     *
  127.  *  Clauses2 is not more informative than Clauses1 if we can not de-   *
  128.  *  rive Clauses1 from Clauses2 using only our absolute rule.          *
  129.  *                                                                     *
  130.  ***********************************************************************/
  131. not_more_informative(Clauses1,Clauses2,Clause1,Clause2):-
  132.     not relcon(Clauses2,Clauses1,Clause2,Clause1),
  133.     !.
  134. /***********************************************************************
  135.  *                                                                     *
  136.  *  Clauses2 also is not more informative than Clauses1 if we can de-  *
  137.  *  rive Clauses2 from Clauses1 using only our absolute rule.          *
  138.  *                                                                     *
  139.  ***********************************************************************/
  140. not_more_informative(Clauses1,Clauses2,Clause1,Clause2):-
  141.     relcon(Clauses1,Clauses2,Clause1,Clause2).
  142. /***********************************************************************
  143.  *                                                                     *
  144.  *  A set of goals are relevant consequents of a set of premises       *
  145.  *  (relative to a database) iff it is possible to derive all of the   *
  146.  *  goals from the set of premises using only the indefeasible rules   *
  147.  *  in the database.  That is, no facts or defeasible rules may be     *
  148.  *  used.                                                              *
  149.  *                                                                     *
  150.  *  The clause 'true' is a relevant consequence of anything.           *
  151.  *                                                                     *
  152.  ***********************************************************************/
  153. relcon(true,_,_,_):- !.
  154. /***********************************************************************
  155.  *                                                                     *
  156.  *  If the condition of the rule is a disjunction, then there is a     *
  157.  *  disjunction error in the rule.  d-Prolog will not compare the      *
  158.  *  conditions of rules if one of the conditions includes disjunc-     *
  159.  *  tions.  We need to know the clause that is the head of the rule    *
  160.  *  when this happens so we will know what to tell the user.           *
  161.  *                                                                     *
  162.  ***********************************************************************/
  163. relcon((_;_),_,Clause,_):-
  164.     disjunction_error(Clause).
  165. relcon(_,(_;_),_,Clause):-
  166.     disjunction_error(Clause).
  167. /***********************************************************************
  168.  *                                                                     *
  169.  *  A conjunction is a relevant consequence of some set of premises if *
  170.  *  each conjunct is a relevant consequence                            *
  171.  *                                                                     *
  172.  ***********************************************************************/
  173. relcon((First,Rest),Premises,Clause1,Clause2):-
  174.     !,
  175.     relcon(First,Premises,Clause1,Clause2),
  176.     relcon(Rest,Premises,Clause1,Clause2).
  177. /***********************************************************************
  178.  *                                                                     *
  179.  *  A clause with a system predicate is a relevant consequence just in *
  180.  *  case it succeeds.                                                  *
  181.  *                                                                     *
  182.  ***********************************************************************/
  183. relcon(Goal,_,_,_):-
  184.     functor(Goal,Predicate,_),
  185.     system(Predicate),
  186.     !,
  187.     Goal.
  188. /***********************************************************************
  189.  *                                                                     *
  190.  *  Every member of the temporary set of premises is a relevant con-   *
  191.  *  sequence.                                                          *
  192.  *                                                                     *
  193.  ***********************************************************************/
  194. relcon(Goal,Premises,_,Clause):-
  195.     belongs(Goal,Premises,Clause),
  196.     !.
  197. /***********************************************************************
  198.  *                                                                     *
  199.  *  If a clause in the consequent of any indefeasible rule in the      *
  200.  *  database, then it is a relevant consquence of the temporary pre-   *
  201.  *  mise set if the antecedent of that rule is a set of relevant con-  *
  202.  *  sequences of the temporary premise set.                            *
  203.  *                                                                     *
  204.  ***********************************************************************/
  205. relcon(Goal,Premises,_,Clause):-
  206.     clause(Goal,Body),
  207.     Body\=true,
  208.     relcon(Body,Premises,Goal,Clause),
  209.     !.
  210. /***********************************************************************
  211.  *                                                                     *
  212.  *  The conmplement of any clause is a contrary of that clause.  Any   *
  213.  *  two clauses which are incompatible are contraries of each other.   *
  214.  *  We use the notion of the contrary of a clause in testing to see    *
  215.  *  is a rule is defeated.                                             *
  216.  *                                                                     *
  217.  ***********************************************************************/
  218. contrary(Clause1,Clause2):-
  219.     incompatible(Clause1,Clause2).
  220. contrary(Clause1,Clause2):-
  221.     incompatible(Clause2,Clause1).
  222. contrary(Clause1,Clause2):-
  223.     comp(Clause1,Clause2).
  224. /***********************************************************************
  225.  *                                                                     *
  226.  *  The complement of an atomic formula is its negation.  The comple-  *
  227.  *  ment of a negative literal is the atomic formula negated in the    *
  228.  *  literal.                                                           *
  229.  *                                                                     *
  230.  ***********************************************************************/
  231. comp(neg Atom,Atom):-
  232.      !.
  233. comp(Atom,neg Atom).
  234. /***********************************************************************
  235.  *                                                                     *
  236.  *  The predicate belongs succeeds if its second argument is a con-    *
  237.  *  junction and its first argument is a conjunct in the conjunction.  *
  238.  *  This predicate will call the disjunction error routine if it de-   *
  239.  *  tects a disjunction in a clause being examined.  The third argu-   *
  240.  *  ment of belongs passes the original clause that originated the     *
  241.  *  disjunctive search for the proposed conjunct.  This information    *
  242.  *  will be needed if the disjunction error routine is invoked.        *
  243.  *                                                                     *
  244.  ***********************************************************************/
  245. belongs(_,(_;_),Clause):-
  246.     disjunction_error(Clause).
  247. belongs(Clause,Clause,_):- !.
  248. belongs(Clause,(Clause,_),_):- !.
  249. belongs(Clause1,(_,Rest),Clause2):-
  250.     !,
  251.     belongs(Clause1,Rest,Clause2).
  252. /***********************************************************************
  253.  *                                                                     *
  254.  *  We invoke the d-Prolog inference engine by using the defeasible    *
  255.  *  query operator @ in front of our goal.                             *
  256.  *                                                                     *
  257.  ***********************************************************************/
  258. @ Goal:- defeasibly_derivable(Goal,[]).
  259. /***********************************************************************
  260.  *                                                                     *
  261.  *  We use the predicate @@ as a way of asking d-Prolog to make a com- *
  262.  *  plete investigation of a goal.  A complete query will tell whe-    *
  263.  *  a goal or any contrary of the goal is either absolutely or defeas- *
  264.  *  ibly derivable.                                                    *
  265.  *                                                                     *
  266.  ***********************************************************************/
  267. @@ Goal:-
  268.     improper(Goal),
  269.     write('Improper argument for @@.'),
  270.     nl,
  271.     write('Argument may not contain a variable, ;, ! or not.'),
  272.     nl,
  273.     !,
  274.     fail.
  275. @@ Goal:-
  276.     Goal,
  277.     !,
  278.     write('definitely, yes -'),
  279.     nl,
  280.     contrary(Goal,Contrary),
  281.     Contrary,
  282.     write('and definitely, no - contradictory'),
  283.     nl.
  284. @@ Goal:-
  285.     contrary(Goal,Contrary),
  286.     Contrary,
  287.     !,
  288.     write('definitely, no - '),
  289.     nl.
  290. @@ Goal:-
  291.     defeasibly_derivable(Goal,[]),
  292.     !,
  293.     write('presumably, yes -'),
  294.     nl,
  295.     contrary(Goal,Contrary),
  296.     defeasibly_derivable(Contrary,[]),
  297.     write('and presumably, no - weakly contradictory'),
  298.     nl.
  299. @@ Goal:-
  300.     contrary(Goal,Contrary),
  301.     defeasibly_derivable(Contrary,[]),
  302.     !,
  303.     write('presumably, no -'),
  304.     nl.
  305. @@ Goal:-
  306.     write('can draw no conclusion'),
  307.     nl.
  308. /***********************************************************************
  309.  *                                                                     *
  310.  *  The complete query operator @@ is to be used only for goals which  *
  311.  *  contain no variables.  A goal with a variable is an improper argu- *
  312.  *  ment for @@.  Any goal containing a cut, not, or a disjunction is  *
  313.  *  also improper.                                                     *
  314.  *                                                                     *
  315.  ***********************************************************************/
  316. improper('!').
  317. improper((not _)) :- !.
  318. improper((_;_)):- !.
  319. improper((First,_)):-
  320.     improper(First),
  321.     !.
  322. improper((_,Rest)):-
  323.     !,
  324.     improper(Rest).
  325. improper(Clause):-
  326.     Clause =.. [Predicate|ArgumentList],
  327.     member(Argument,ArgumentList),
  328.     var(Argument).
  329. /***********************************************************************
  330.  *                                                                     *
  331.  *  The predicate member succeeds if its second argument is a list     *
  332.  *  and is first argument is a member of that list.                    *
  333.  *                                                                     *
  334.  ***********************************************************************/
  335. member(X,[X|_]).
  336. member(X,[_|Y]):-
  337.     member(X,Y).
  338. /***********************************************************************
  339.  *                                                                     *
  340.  *  When we list a predicate, we also want to see the defeasible rules *
  341.  *  and defeaters for this predicate, any rules or defeaters for the   *
  342.  *  negation of this predicate, and any clauses incompatible with      *
  343.  *  clause containing this predicate.  The list operation provides     *
  344.  *  this information.                                                  *
  345.  *                                                                     *
  346.  ***********************************************************************/
  347. list(Predicate):-
  348.     listing(Predicate),
  349.     fail.
  350. list(Predicate):-
  351.     clause(neg Atom,Body),
  352.     functor(Atom,Predicate,_),
  353.     pprint(neg Atom,' :-',Body),
  354.     fail.
  355. list(Predicate):-
  356.     (Head := Body),
  357.     functor(Head,Predicate,_),
  358.     pprint(Head,' :=',Body),
  359.     fail.
  360. list(Predicate):-
  361.     ((neg Atom) := Body),
  362.     functor(Atom,Predicate,_),
  363.     pprint(neg Atom,' :=',Body),
  364.     fail.
  365. list(Predicate):-
  366.     (Head :^ Body),
  367.     functor(Head,Predicate,_),
  368.     pprint(Head,' :^',Body),
  369.     fail.
  370. list(Predicate):-
  371.     ((neg Atom) :^ Body),
  372.     functor(Atom,Predicate,_),
  373.     pprint(neg Atom,' :^',Body),
  374.     fail.
  375. list(Predicate):-
  376.     incompatible(Clause1,Clause2),
  377.     functor(Clause1,Predicate,_),
  378.     write('incompatible('),
  379.     write(Clause1),
  380.     write(','),
  381.     write(Clause2),
  382.     write(').'),
  383.     nl,
  384.     fail.
  385. list(Predicate):-
  386.     incompatible(Clause1,Clause2),
  387.     functor(Clause2,Predicate,_),
  388.     write('incompatible('),
  389.     write(Clause2),
  390.     write(','),
  391.     write(Clause1),
  392.     write(').'),
  393.     nl,
  394.     fail.
  395. list(_).
  396. /***********************************************************************
  397.  *                                                                     *
  398.  *  The pprint procedure pretty-prints rules for us.  It is an essen-  *
  399.  *  tial subroutine of the list procedure.  The pprint procedure has   *
  400.  *  components, one of arity 3, one of arity 2, and one of arity 1.    *
  401.  *  The component of arity 3 take the head, operator, and body of a    *
  402.  *  rule as arguments, writes the head, and passes the operator and    *
  403.  *  body to the component of arity 2.  The component of arity 2 writes *
  404.  *  the operator of the rule, then terminates pretty-printing in an    *
  405.  *  appropriate way if the body of the rule is the special predicate   *
  406.  *  true.  If the body of the rule is anything else, this component    *
  407.  *  passes the body of the rule along to the component of arity 1 for  *
  408.  *  pretty-printing.                                                   *
  409.  *                                                                     *
  410.  ***********************************************************************/
  411. pprint(Head,Operator,Body):-
  412.     !,
  413.     write(Head),
  414.     pprint(Operator,Body).
  415. /***********************************************************************
  416.  *                                                                     *
  417.  *  The next clause completes the pretty-printing of a negative fact   *
  418.  *  by printing a period.  The only kind of rule list will pass to     *
  419.  *  pprint that has :- as operator and true as body is a negative      *
  420.  *  fact.                                                              *
  421.  *                                                                     *
  422.  ***********************************************************************/
  423. pprint(' :-',true):-
  424.     !,
  425.     write(' .'),
  426.     nl.
  427. pprint(' :-',Clause):-
  428.     !,
  429.     write(' :-'),
  430.     pprint(Clause).
  431. /***********************************************************************
  432.  *                                                                     *
  433.  *  The next clause processes a defeasible rule or defeater with an    *
  434.  *  empty antecedent, i.e., with the special predicate true as its     *
  435.  *  body.  It indents and prints 'true', then finishes by printing a   *
  436.  *  period.                                                            *
  437.  *                                                                     *
  438.  ***********************************************************************/
  439. pprint(Operator,Clause):-
  440.     write(Operator),
  441.     Clause==true,
  442.     !,
  443.     nl,
  444.     write('    true.'),
  445.     nl.
  446. pprint(Operator,Clause):-
  447.     pprint(Clause).
  448. /***********************************************************************
  449.  *                                                                     *
  450.  *  The arity 1 component of pprint breaks a conjunction into its in-  *
  451.  *  vidual conjuncts, then prints each conjunct in a suitable format.  *
  452.  *                                                                     *
  453.  ***********************************************************************/
  454. pprint((First,Rest)):-
  455.     !,
  456.     nl,
  457.     write('    '),
  458.     write(First),
  459.     write(' ,'),
  460.     pprint(Rest).
  461. pprint(Clause):-
  462.     nl,
  463.     write('    '),
  464.     write(Clause),
  465.     write(' .'),
  466.     nl.
  467. /***********************************************************************
  468.  *                                                                     *
  469.  *  The predicate rescind is a d-Prolog counterpart of the Prolog      *
  470.  *  predicate retractall.  Besides ordinary Prolog rules, it also      *
  471.  *  removes all negations, defeasible rules and defeaters from the     *
  472.  *  database.                                                          *
  473.  *                                                                     *
  474.  ***********************************************************************/
  475. rescind(Clause):-
  476.     retractall(Clause),
  477.     retractall((neg Clause)),
  478.     retractall((:-(Clause,_))),
  479.     retractall((:-(neg Clause,_))),
  480.     retractall((:=(Clause,_))),
  481.     retractall((:=(neg Clause,_))),
  482.     retractall((:^(Clause,_))),
  483.     retractall((:^(neg Clause,_))).
  484. retractall(Clause):-
  485.     retract(Clause),
  486.     fail.
  487. retractall(_).
  488. /***********************************************************************
  489.  *                                                                     *
  490.  *  The syntax of d-Prolog does not allow disjunctions.  Otherwise,    *
  491.  *  the relcon test would require too much computation.  It is left    *
  492.  *  to the d-Prolog programmer to write programs that do not use dis-  *
  493.  *  junction.  If the d-Prolog inference engine encounters a disjunc-  *
  494.  *  tion at a crucial point in its computation, it will invoke the     *
  495.  *  disjunction_error procedure defined below.  This routine will      *
  496.  *  locate all disjunction errors for the goal that invoked the dis-   *
  497.  *  jundtion error procedure and display them.                         *
  498.  *                                                                     *
  499.  ***********************************************************************/
  500. disjunction_error(Clause):-
  501.     nl,
  502.     write('d-Prolog Syntax Error'),
  503.     nl,
  504.     nl,
  505.     clause(Clause,Body),
  506.     bad_syntax(Body),
  507.     pprint(Clause,' :-',Body),
  508.     fail.
  509. disjunction_error(Clause):-
  510.     nl,
  511.     (Clause := Body),
  512.     bad_syntax(Body),
  513.     pprint(Clause,' :=',Body),
  514.     fail.
  515. disjunction_error(Clause):-
  516.     nl,
  517.     (Clause :^ Body),
  518.     bad_syntax(Body),
  519.     pprint(Clause,' :^',Body),
  520.     fail.
  521. disjunction_error(_):-
  522.     write(
  523. 'This clause contains an illegal disjunction.  Evaluation aborted.'
  524.           ),
  525.     nl,
  526.     abort.
  527. /***********************************************************************
  528.  *                                                                     *
  529.  *  The following procedure is used by the disjunction_error routine   *
  530.  *  to determine whether a clause contains a disjunction.              *
  531.  *                                                                     *
  532.  ***********************************************************************/
  533. bad_syntax((_;_)) :- !.
  534. bad_syntax(((_;_),_)) :- !.
  535. bad_syntax((_,Rest)):-
  536.     !,
  537.     bad_syntax(Rest).
  538. /***********************************************************************
  539.  *                                                                     *
  540.  *  The following procedures will reconsult a d-Prolog database with-  *
  541.  *  out losing defeasible rules, defeaters, or negative rules that are *
  542.  *  divided because they have different d-Prolog predicates. This      *
  543.  *  facility expects the d-Prolog database to be on the selected disk  *
  544.  *  and to have the .DPL extension. The parameter passed to reload     *
  545.  *  should be the name of the file without any extension.              *
  546.  *                                                                     *
  547.  ***********************************************************************/
  548. reload(Filename) :-
  549.     string_term(FileString,Filename),
  550.     concat([FileString,$.DPL$],NewFilename),
  551.     open(Handle,NewFilename,r),
  552.     repeat,
  553.     get_term(Handle,Term),
  554.     rescind_previous_clauses(Term),
  555.     add_to_memory(Term),
  556.     Term == end_of_file,
  557.     close(Handle),
  558.     abolish(have_seen_this_predicate_before/2).
  559. get_term(Handle,Term) :-
  560.     read(Handle,Term),
  561.     !.
  562. get_term(_,end_of_file).
  563. /****************************************************************
  564.  *                                                              *
  565.  *  rescind_previous_clauses(Term)                              *
  566.  *    checks to see if any term with the d-Prolog predicate of  *
  567.  *    Term has already been loaded. If so, or if we have reach- *
  568.  *    ed the end of the file, nothing is done. Otherwise, the   *
  569.  *    d-Prolog predicate of Term is rescinded. Remember that    *
  570.  *    the d-Prolog predicate of a term may be different from    *
  571.  *    the Prolog predicate. For example, the Prolog prdicate of *
  572.  *    'neg flies(X) :- penguin(X)' is 'neg' and the Prolog pre- *
  573.  *    dicate of 'flies(X) := bird(X)' is ':='.                  *
  574.  *                                                              *
  575.  ***************************************************************/
  576. rescind_previous_clauses(end_of_file) :- !.
  577. rescind_previous_clauses(Term) :-
  578.     functor(Term,F,2),
  579.     member(F,[(:-),':=',':^']),
  580.     arg(1,Term,Head),
  581.     !,
  582.     rescind_previous_clauses(Head).
  583. rescind_previous_clauses(incompatible(X,Y)) :-
  584.     !,
  585.     rescind_previous_clauses(X),
  586.     rescind_previous_clauses(Y).
  587. rescind_previous_clauses('neg' Term) :-
  588.     !,
  589.     rescind_previous_clauses(Term).
  590. rescind_previous_clauses(Term) :-
  591.     functor(Term,Predicate,Arity),
  592.     have_seen_this_predicate_before(Predicate,Arity),
  593.     !.
  594. rescind_previous_clauses(Term) :-
  595.     functor(Term,Predicate,Arity),
  596.     make_dummy_clause(Arity,Predicate,Dummy),
  597.     rescind(Dummy),
  598.     asserta(have_seen_this_predicate_before(Predicate,Arity)).
  599. add_to_memory(end_of_file) :- !.
  600. add_to_memory(Term) :-
  601.     assertz(Term).
  602. /****************************************************************
  603.  *                                                              *
  604.  *  make_dummy_clause(N,[Predicate],Dummy)                      *
  605.  *    produces a clause with Predicate as the functor and N     *
  606.  *    many variables as arguments. This is used with rescind    *
  607.  *    to eliminate clauses that are being reloaded.             *
  608.  *                                                              *
  609.  ****************************************************************/
  610. make_dummy_clause(N,Predicate,Dummy) :-
  611.     make_variable_list(N,[],VariableList),
  612.     Dummy =.. [Predicate|VariableList],
  613.     !.
  614. make_variable_list(0,X,X).
  615. make_variable_list(N,OldList,VariableList) :-
  616.     M is N - 1,
  617.     make_variable_list(M,[_|OldList],VariableList).
  618. /***************************************************************
  619.  *                                                              *
  620.  *  redit will edit then reload a d-Prolog database. The same   *
  621.  *  restrictions on parameter and filename extension apply to   *
  622.  *  redit as to reload.                                         *
  623.  *                                                              *
  624.  ****************************************************************/
  625. redit(Filename) :-
  626.     string_term(FileString,Filename),
  627.     concat([FileString,$.DPL$],NewFilename),
  628.     edit(NewFilename),
  629.     reload(Filename).
  630.